home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / sbprolog / amiga / v3_1 / sbp3_1e.lzh / READINT.PL < prev    next >
Text File  |  1991-10-31  |  2KB  |  48 lines

  1. /* From the book PROLOG PROGRAMMING IN DEPTH
  2.    by Michael A. Covington, Donald Nute, and Andre Vellino.
  3.    Copyright 1988 Scott, Foresman & Co.
  4.    Non-commercial distribution of this file is permitted. */
  5.  
  6. /* READINT.PL */
  7. /* First attempt at a general-purpose numeric input routine. */
  8.  
  9. /* Requires procedure READSTRING defined in file READSTR.PL */
  10. :- ( clause(readstring(_),_) ; consult('readstr.pl') ).
  11.  
  12. /**********************************************************************
  13.  * readinteger(Result)                                                *
  14.  *   Accepts a string from the user and interprets it as an integer.  *
  15.  *   Leading, trailing, and embedded blanks are permitted.            *
  16.  **********************************************************************/
  17.  
  18. readinteger(Result) :- readstring(S),
  19.                        readinteger_aux(S,0,Result).
  20.  
  21. readinteger_aux([32|T],SoFar,Result) :-   /* ignore blanks */
  22.                          !,
  23.                          readinteger_aux(T,SoFar,Result).
  24.  
  25. readinteger_aux([H|T],SoFar,Result) :-    /* process a digit */
  26.                          readinteger_value(H,V),
  27.                          !,
  28.                          NewSoFar is SoFar*10 + V,
  29.                          readinteger_aux(T,NewSoFar,Result).
  30.  
  31. readinteger_aux([],Result,Result) :- !.   /* string empty, */
  32.                                           /* return result */
  33.  
  34. readinteger_aux(_,_,Result) :-            /* unrecognized character */
  35.                          write('Number expected. Try again:'),
  36.                          readinteger(Result).
  37.  
  38. readinteger_value(48,0).    /* Table converting ASCII codes */
  39. readinteger_value(49,1).    /* of digits to numeric values  */
  40. readinteger_value(50,2).
  41. readinteger_value(51,3).
  42. readinteger_value(52,4).
  43. readinteger_value(53,5).
  44. readinteger_value(54,6).
  45. readinteger_value(55,7).
  46. readinteger_value(56,8).
  47. readinteger_value(57,9).
  48.